home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Cream of the Crop 1
/
Cream of the Crop 1.iso
/
EDUCATE
/
SPECTRM2.ARJ
/
SINE.FOR
< prev
next >
Wrap
Text File
|
1992-04-22
|
4KB
|
164 lines
* SINE.FOR
* Sinewave Generation Program
* David E. Hess
* Fluid Flow Group - Process Measurements Division
* Chemical Science and Technology Laboratory
* National Institute of Standards and Technology
* April 15, 1992
* The purpose of this routine is to use the computer to generate
* a known function of time (a sinewave) and to store the output
* in a data file that may be read by SPECTRUM. The routine then
* simulates the sampling process by prompting for the various
* sampling parameters.
IMPLICIT REAL*4 (A-H,O-Z), INTEGER*2 (I-N)
PARAMETER (NUMO=2,NUMO2=3,NMAX=16384)
INTEGER*2 GAIN(0:7)
INTEGER*2 NDATA[ALLOCATABLE,HUGE](:)
INTEGER*4 IRSIZE,I,IDELTMS
REAL*4 T[ALLOCATABLE,HUGE](:)
REAL*4 X[ALLOCATABLE,HUGE](:)
CHARACTER*1 FIRST
CHARACTER*4 FLNM
CHARACTER*8 FILNAM
* Initialization
ICHANS=1
PI=2.0*ASIN(1.0)
VOFST=20.0/4096.0
GAIN=0
* Get the input parameters.
WRITE (*,'(1X,A\)') 'Enter the amplitude of the sinewave : '
READ (*,*) AMP
WRITE (*,'(1X,A\)') 'Enter the frequency of the sinewave : '
READ (*,*) FREQ
WRITE (*,'(1X,A\)') 'Enter the phase (in degrees) : '
READ (*,*) PHASE
WRITE (*,'(1X,A\)') 'Enter DC value : '
READ (*,*) DC
WRITE (*,'(1X,A\)') 'Enter delta T secs. (1.0/Sample Rate) : '
READ (*,*) DELT
30 WRITE (*,'(1X,A\)') 'Enter # of points per record (N) : '
READ (*,*) N
* N less than or equal to NMAX error checking.
IF (N .GT. NMAX) THEN
WRITE (*,'(/1X,A,I5/)')
+ '# of points per record <= ',NMAX
GO TO 30
ENDIF
* Power of two error checking.
FN=FLOAT(N)
ITST=NINT(ALOG10(FN)/ALOG10(2.0))
ITST2=INT(2**ITST)-N
IF (ITST2 .NE. 0) THEN
WRITE (*,'(/1X,A,I5,A/1X,A/)') 'You have entered ',
+ N,' data points.','# data points must be a power of 2.'
GO TO 30
ENDIF
* Allocate space for the NDATA, T and X arrays.
ALLOCATE (NDATA(N), T(N), X(N), STAT=IERR)
IF (IERR .NE. 0)
+ STOP 'Not enough storage for data. Aborting ...'
WRITE (*,'(1X,A\)') 'Enter # of records (NUMREC) : '
READ (*,*) NUMREC
40 WRITE (*,'(1X,A\)') 'Enter output file name (4 chars) : '
READ (*,'(A)') FLNM
* Convert to uppercase and check first character alphabetic.
DO J=4,1,-1
FIRST=FLNM(J:J)
IF (ICHAR(FIRST) .GE. 97 .AND. ICHAR(FIRST) .LE. 122) THEN
IHOLD=ICHAR(FIRST)-32
FIRST=CHAR(IHOLD)
FLNM(J:J)=FIRST
ENDIF
ENDDO
IF (ICHAR(FIRST) .LT. 65 .OR. ICHAR(FIRST) .GT. 90) THEN
WRITE (*,'(/1X,A,A,A/1X,A,A,A/1X,A/)')
+ 'Filename ',FLNM,' began with',
+ 'the nonalphabetic character ',FIRST,'.',
+ 'Re-enter the filename correctly.'
GO TO 40
ENDIF
FILNAM=FLNM // '.DAT'
IRSIZE=ICHANS*N*2
IDELTMS=NINT(DELT*1.0E+06)
PHASRD=PHASE*2.0*PI/360.0
* Write the data in the form of binary numbers to a data
* file that may be read by SPAD.
OPEN (NUMO,FILE=FILNAM,STATUS='UNKNOWN',ACCESS='SEQUENTIAL',
+ FORM='BINARY')
WRITE (NUMO) ICHANS,IRSIZE,NUMREC,IDELTMS
WRITE (NUMO) (GAIN(I),I=0,7)
* Put message on screen.
WRITE (*,'(/////////////////////16X,
+ ''S I N E W A V E C R E A T I O N U T I L I T Y'')')
WRITE (*,'(/25X,''Creating '',A,'' now.''/)') FILNAM
DO IB=1,NUMREC
* Vary the phase of the sinewave for different records to
* simulate the effect of noncontiguous chunks of time in
* the sampling process.
PHASE=PHASRD+FLOAT(IB-1)/FLOAT(NUMREC-1)*2.0*PI
* Generate the sinewave.
DO I=0,N-1
T(I+1)=FLOAT(I)*DELT
X(I+1)=DC+AMP*SIN(2.0*PI*FREQ*T(I+1)+PHASE)
NDATA(I+1)=INT(X(I+1)/VOFST)
ENDDO
* Display record number message.
IF (IB .EQ. 1) THEN
WRITE (*,50) IB
50 FORMAT (25X,'Writing Record ',I4.4)
ELSE
WRITE (*,60) IB
60 FORMAT ('+',24X,'Writing Record ',I4.4)
ENDIF
* Output the results to the unformatted file.
WRITE (NUMO) (NDATA(I),I=1,N)
* Put the results of the first record in a formatted file.
IF (IB .EQ. 1) THEN
OPEN (NUMO2,FILE='SINT.PRN',STATUS='UNKNOWN')
WRITE (NUMO2,'(G17.7,2X,G17.7)') (T(I),X(I),I=1,N)
CLOSE (NUMO2,STATUS='KEEP')
ENDIF
ENDDO
CLOSE (NUMO,STATUS='KEEP')
WRITE(*,'( )')
STOP ' Program terminated successfully.'
END